home *** CD-ROM | disk | FTP | other *** search
- ;================================================
- ; PROGRAM WC Version 1.1 by Dave Whitman
- ;
- ; Filter to count words, lines and characters.
- ; Based loosely on Kernighan and Ritchie, page 18.
- ;
- ; Syntax: WC [/w] [/l] [/c]
- ;
- ; /w = unlabeled word count
- ; /l = unlabeled line count
- ; /c = unlabeled character count
- ; none = combined counts, with labels
- ;
- ; The three options may be present in any combination.
- ; Regardless of option order, the selected counts will
- ; be in the following order:
- ; words
- ; lines
- ; characters
- ;
- ; Requires DOS 2.0, will abort under earlier versions.
- ;====================================================
-
- ;============
- ; Equates
- ;============
-
- @read equ 3FH ;read file/device
- @chrin equ 06H ;get char from stdin
- @chrout equ 02H ;send char to stdout
- @dosver equ 30H ;get dos version
- @prnstr equ 09H ;print string
-
- stdin equ 0000H ;standard input
- w equ 01H ;flag value for word option
- l equ 02H ;flag value for line option
- c equ 04H ;flag value for char option
- yes equ 0FFH ;boolean value
- no equ 00H ; "
- \n equ 0DH ;newline char
- \t equ 09H ;tab char
- \l equ 0AH ;linefeed char
-
- param_count equ [80H]
- param_area equ [81H]
-
- main proc far
- call setup ;check dos, parse options
- call buf_in ;count w, l, c from std i/o
- call output ;send requested output
- int 20H ;and return to dos
- endp
-
- ;======================================
- ; SUBROUTINE SETUP
- ; Checks for proper DOS, parses options
- ;======================================
- setup proc near
-
- mov ah, @dosver ;what dos are we under?
- int 21H
- cmp al, 2 ;2.0 or over?
- jae a1 ;yes, skip
-
- mov ah, @prnstr ;no, bitch
- mov dx, offset(baddos)
- int 21H
- pop ax ;reset stack
- int 20H ;and exit
-
- a1 xor ch,ch ;cx <== param count
- mov cl, param_count ; "
- cmp cl, 00H ;any params?
- je aexit ;exit if none
-
- mov di, offset(param_area) ;scan for options
- a2 mov al, '/' ;will be marked with /
- repnz
- scasb
- jnz aexit ;reached end
-
- mov al, [di] ;get option char
- and al, 0DFH ;guarantees upper case
-
- cmp al, 'W' ;words?
- jne a3 ;nope
- orb options, w ;yes, set flag
- jmps a2 ;and loop
-
- a3 cmp al, 'L' ;lines?
- jne a4 ;nope
- orb options, l ;yes, set flag
- jmps a2 ;and loop
-
- a4 cmp al, 'C' ;characters?
- jne a2 ;nope, just loop
- orb options, c ;yes, set flag
- jmps a2 ;and loop
-
- aexit ret
-
- baddos db 'This program requires DOS 2.0!' 0DH, 0AH, '$'
- endp
-
- ;=========================================
- ; SUBROUTINE BUF_INPUT
- ; Inputs data by sector, sends it one char
- ; at a time for counting.
- ;==========================================
-
-
- buf_in proc near
-
- movb inword, no ;not currently in a word
-
- bu1 mov ah, @read ;read
- mov bx, stdin ;from stdin
- mov cx, 512 ;one sector's worth
- mov dx, offset(buffer)
- int 21H
- cmp ax, 00H ;test for EOF
- jz buexit ;if so, done
-
- mov cx,ax ;cx <== number chars read
- mov si, offset(buffer)
- bu2 lodsb ;al <== next char from buffer
- call count ;update totals
- loop bu2
- jmps bu1
- buexit ret
- endp
-
- ;=============================================
- ;SUBROUTINE COUNT
- ;Counts words, lines and characters as per K&R
- ;=============================================
- count proc near
- addw clow,0001H ;bump # of chars
- jae b1 ;no carry? skip
- incw chigh ;handle carry
-
- ;in the following, note use of ADD to increment
- ;doublewords. INC does not affect Carry Flag.
-
- b1 cmp al, \n ;is it a newline?
- jne b2 ;no, skip
- addw llow,0001H ;bump # of lines
- jae b2 ;no carry? skip
- incw lhigh ;handle carry
-
- b2 cmp al, \n ;newline or
- je b3
- cmp al, \t ;tab or
- je b3
- cmp al, \l ;linefeed or
- je b3
- cmp al, ' ' ;blank,
- je b3 ;then skip
-
- ;none of the above
- cmpb inword, yes ;already in a word?
- je b4 ;yes, return
- movb inword, yes ;if not, we are now.
- addw wlow,0001H ;bump word count
- jae b4 ;no carry? return
- incw whigh ;handle carry
- jmps b4 ;return
-
- ;any of the above
- b3 movb inword, no
- b4 ret
- endp
-
- ;=====================================
- ; SUBROUTINE OUTPUT
- ; Prints results, modified by options.
- ;=====================================
- output proc near
-
- cmpb options, 00H ;any options?
- jne c1 ;yes, skip label
- mov ah, @prnstr ;print label for word count
- mov dx, offset(word_label)
- int 21H
- jmps c1a ;print count
-
- c1 testb options, W ;/w option?
- jz c2 ;nope, skip
- c1a mov di, whigh ;get doubleword word count
- mov si, wlow ; in di:si
- call printdd ;convert and print it.
- call newline
-
- c2 cmpb options, 00H ;any options?
- jne c3 ;yes, skip label
- mov ah, @prnstr ;print label for line count
- mov dx, offset(line_label)
- int 21H
- jmps c3a ;print count
-
- c3 testb options, L ;/l option?
- jz c4 ;nope, skip
- c3a mov di, lhigh ;get doubleword line count
- mov si, llow ; in di:si
- call printdd ;convert and print it
- call newline
-
- c4 cmpb options, 00H ;any options?
- jne c5 ;yes, skip label
- mov ah, @prnstr ;print label for char count
- mov dx, offset(char_label)
- int 21H
- jmps c5a ;print count
-
- c5 testb options, C ;/c option?
- jz c6 ;nope, skip
- c5a mov di, chigh ;get doubleword char count
- mov si, clow ; in di:si
- call printdd ;convert and print it
- call newline
-
- c6 ret
-
- word_label db 'Words: $'
- line_label db 'Lines: $'
- char_label db 'Chars: $'
- endp
-
- ;=========================
- ; SUBROUTINE NEWLINE
- ; Prints a CR/LF to stdout
- ;=========================
- newline proc near
- mov ah, @prnstr
- mov dx, offset(crlf)
- int 21H
- ret
- crlf db 0DH, 0AH, '$'
- endp
-
- ;=========================================================
- ; SUBROUTINE PRINTDD
- ; This less-than-comprehensible routine was swiped verbatim
- ; from Ted Reuss's disassembly of John Chapman's sorted
- ; disk directory program. The routine converts a 32 bit
- ; integer in DI:SI to ASCII digits and sends them to STDOUT.
- ;==========================================================
-
- PRINTDD PROC NEAR ;Prints a 32 bit integer in DI:SI
- XOR AX,AX ;Zero out the
- MOV BX,AX ; working
- MOV BP,AX ; registers.
- MOV CX,32 ;# bits of precision
- J1 SHL SI
- RCL DI
- XCHG BP,AX
- CALL J6
- XCHG BP,AX
- XCHG BX,AX
- CALL J6
- XCHG BX,AX
- ADC AL,0
- LOOP J1
- MOV CX,1710H ;5904 ?
- MOV AX,BX
- CALL J2
- MOV AX,BP
- J2 PUSH AX
- MOV DL,AH
- CALL J3
- POP DX
- J3 MOV DH,DL
- SHR DL ;Move high
- SHR DL ; nibble to
- SHR DL ; the low
- SHR DL ; position.
- CALL J4
- MOV DL,DH
- J4 AND DL,0FH ;Mask low nibble
- JZ J5 ;If not zero
- MOV CL,0
- J5 DEC CH
- AND CL,CH
- OR DL,'0' ;Fold in ASCII zero
- SUB DL,CL
-
- MOV AH, @CHROUT ;Print next digit
- INT 21H
-
- RET ;Exit to caller
- ENDP
-
- J6 PROC NEAR
- ADC AL,AL
- DAA
- XCHG AL,AH
- ADC AL,AL
- DAA
- XCHG AL,AH
- RET
- ENDP
-
- ;=================
- ;GLOBAL VARIABLES
- ;=================
- options db 00H ;byte of option flags
- inword db 00H ;flag: yes indicates scan is within a word
- wlow db 00H, 00H ;low part of doubleword word count
- whigh db 00H, 00H ;high " " " " "
- llow db 00H, 00H ;low part of doubleword line count
- lhigh db 00H, 00H ;high " " " " "
- clow db 00H, 00H ;low part of doubleword char count
- chigh db 00H, 00H ;high " " " " "
- buffer ;input buffer